<--- %%NOBANNER%% --> npair2means.sas
 BackForward

/*-------------------<-- Start of Description -->--------------------\
| Nonparametric Analysis of 2-Sample means with equal variances:     |
| Compute the Hodges-Lehmann estimator and confidence interval for   |
| the Walsh Averages of the location differences between the two     |
| samples;                                                           |
| Note: the tiesadj options doesn't apply to unpaired 2-sample means,|
|       it only applies to paired 2-sample location problems; if     |
|       option is specified "T" for Unpaired 2-sample means, it won't|
|       give you any error messages, but it just won't do anything to|
|       adjust ties.                                                 |
|--------------------<-- End of Description -->----------------------|
|--------------------------------------------------------------------|
|--------------<-- Start of Files or Arguments Needed -->------------|
|  The following parameters are needed for the macro:                |
|     indata  = Input dataset;                                       |
|     class   = Class variables;                                     |
|               this will set the macro to compare the highest order |
|               of the group vs the lower group: for example, if the |
|               class has two groups: 1 and 2, it will compare group |
|               2 vs 1 (group 2 - 1); if character class variable, it|
|               will use the alphabetic order, still the group with  |
|               higher order - the one with lower order;             |
|               So if you want to compare the treatment effect,assign|
|               the treatment group with a higher group;             |
|     trtgrp  = Treatment group Indicator: a value to represent      |
|               treatment;                                           |
|     AVAR    = Analysis variable;                                   |
|     ALPHA   = 100*(1-ALPHA)% level for the two-sided confidence    |
|               interval; default is 0.05;                           |
|     tail    = two-sided or one sided confidence interval; default  |
|               is 2;                                                |
|     option  = Unpaired or Paired, default if Unpaired;             |
|     matchby = Paired Variable: if paired sample, the variable used |
|               to match the other pair;                             |
|        Note: A matchyby variable is required for Paired Sample;    |
|              but for Unpaired sample, matchby variable is not      |
|              needed;                                               |
|     theta0  = the value of treatement effects:                     |
|               H0: (group2 - group1)=theta0;                        |
|               default is 0;                                        |
|     bound   = lower bound or upper bound of one sized confidence   |
|               interval;                                            |
|     tiesadj = t or f; Ties adjustment; default is false;           |
|     outdata = output data set;                                     |
|  Note: parameters "matchby" and "theta0" is only available for     |
|     paired 2-sample location problems.                             |
|---------------<-- End of Files or Arguments Needed -->-------------|
|--------------------------------------------------------------------|
|----------------<-- Start of Example and Usage -->------------------|
| Test the macro using Example 2 on page 75 of "Nonparametric        |
| Statistical Methods" by Hollander & Wolfe. The Hodges-Lehman       |
| estimate is 0.305. The 90% confidence interval is (-.08, .72).     |
| Example                                                            |
| data hw_ex2;                                                       |
|    input grp val;                                                  |
| cards;                                                             |
| 1 0.80                                                             |
| 1 0.83                                                             |
| 1 1.89                                                             |
| 1 1.04                                                             |
| 1 1.45                                                             |
| 1 1.38                                                             |
| 1 1.91                                                             |
| 1 1.64                                                             |
| 1 0.73                                                             |
| 1 1.46                                                             |
| 2 1.15                                                             |
| 2 0.88                                                             |
| 2 0.90                                                             |
| 2 0.74                                                             |
| 2 1.21                                                             |
| ;                                                                  |
| run;                                                               |
| %npar2mean(indata=hw_ex2, class=grp, avar=val, alpha=0.05, tail=2, |
|            bound=low, outdata=test);                               |
|*******************************************************************;|
| Test of example from page 15 of Douglas Wolfe's notes.             |
| The Hodges-Lehmann estimate is 45.5.                               |
| data dw_p15;                                                       |
|    input grp val;                                                  |
| cards;                                                             |
| 1 133                                                              |
| 1 191                                                              |
| 1 118                                                              |
| 2 254                                                              |
| 2 171                                                              |
| 2 345                                                              |
| 2 134                                                              |
| 2 190                                                              |
| 2 106                                                              |
| ;                                                                  |
| run;                                                               |
| %npar2mean(indata=dw_p15, class=grp, trtgrp=1, avar=val,           |
|            alpha=0.05, tail=2, bound=low, outdata=test);           |
| The Result should look like the following:                         |
|    Two Sided Test on Group 2-1:                                    |
|    H0: treatment = 0 vs H1: treatment <> 0;                        |
|          Median of Walsh Averages   = -45.5                        |
|          Lower 95% confidence bound = -227                         |
|          Upper 95% confidence bound = 85                           |
|********************************************************************|
| data hw_ex2;                                                       |
|    input subject grp $ val @@;                                     |
| cards;                                                             |
| 1 x 270 1 y 525 2 x 150 2 y 570 3 x 270 3 y 190 4 x 420 4 y 395    |
| 5 x 202 5 y 370                                                    |
| ;                                                                  |
| run;                                                               |
| %npar2mean(indata=hw_ex2, class=grp, trtgrp='y', matchby=subject,  |
|            avar=val, alpha=0.124, tail=2,bound=low, option=Paired, |
|            outdata=test);                                          |
|********************************************************************|
| Usage: %npar2mean(indata=,class=,avar=,alpha=0.05, tail=2,         |
|                   bound=both, outdata=);                           |
| Reference: Hollander M and Wolfe DA, "Nonparmetric Statistical     |
|            Methods," pp 75-79.                                     |
\-------------------<-- End of Example and Usage -->----------------*/
%macro npar2mean(indata=,class=,trtgrp=, avar=,alpha=0.05,tail=2,theta0=0,
                 tiesadj=,bound=both,option=unpaired,matchby=,outdata=);
/*--------------------------------------------\
| Author:  Duo Zhou;                          |
| Created: 2-13-2002 9:30pm;                  |
| Purpose: Nonparametric Analysis: Median and |
|          Confidence Interval of the Walsh   |
|          Averages;                          |
\--------------------------------------------*/
%local _maxn _minn _lcl _ucl _mwalsh _pvalue _uhead _op _grpn _grplist _varchk
       _varlen _trtchk _byn _minimumn _tmplast_;
%let _lcl=0; %let _ucl=0; %let _op=; %let _tmplast_=&syslast;
%if (%index(&trtgrp,%str(%'))) or (%index(&trtgrp,%str(%"))) %then %do;
   %let trtgrp=%sysfunc(dequote(&trtgrp));
%end;
options SKIP=0 FORMDLIM=" "; title; footnote;
%let _linesize = %SYSFUNC(GETOPTION(linesize));
proc sql noprint;
   select count(distinct &class) into: _grpn
   from &indata
   where &class is not missing;
quit;
%if (%quote(&_grpn) ne %quote(2)) %then %do;
   %put ==> Alert! Sorry, I can only compare two sample locations, I can%str(%')t deal with;
   %put +++        &_grpn samples.;
   %goto finish;
%end;
%if (%index(%quote(%upcase(&option)), PAIR)) and
    (not %index(%quote(%upcase(&option)), UN)) and
    (%quote(&matchby) eq) %then %do;
   %put ==> Alert! Sorry, I need a match variable to calculate the paired differences in order to compare;
   %put +++        paired two sample Locations;
   %goto finish;
%end;
proc contents data=&indata out=_vchecktmp noprint;
run;
proc sql noprint;
   select type, length into: _varchk, :_varlen
   from _vchecktmp
   where name="&class";
quit;
/* If treatment group indicator isn't given, sort the class variable in ascending
   alphabetic order, use larger group value as treatment; */
%if (%quote(&trtgrp) eq) %then %do;
   proc sql noprint;
      create table _shldata as
      select *
      from &indata
      where &class is not missing
      order by &class;

      select distinct &class into: _grplist separated by ','
      from _shldata
      where &class is not missing;
   quit;
%end;
/* If treatment indicator is given, use this group as treatment; */
%else %do;
   %let _trtchk=;
   proc sql noprint;
      select &class into: _trtchk
      from &indata
      /* &trtgrp refer to a value, but &class is referring to a data variable; */
      %if (%quote(&_varchk) eq %quote(1)) %then %do;
      where &class = &trtgrp
      %end;
      %else %do;
      where upcase(&class)="%upcase(&trtgrp)"
      %end;;
   quit;
   /* Check the class variable to see if it has a treatment group, otherwise error; */
   %if (%quote(&_trtchk) ne) %then %do;
      /* The treatment group will be the 2nd group, the control group will be the 1st; */
      proc sql noprint;
         create table _shldata as
         select *,
                %if (%quote(&_varchk) eq %quote(1)) %then %do; (1+(&class=&trtgrp)) as _cgrp %end;
                %else %do; (1+(upcase(&class)="%upcase(&trtgrp)")) as _cgrp %end;
         from &indata
         where &class is not missing
         order by _cgrp;

         %if (%quote(&_varchk) eq %quote(1)) %then %do;
         select distinct &class as &class,
         %end;
         %else %do;
         select distinct upcase(&class) as &class,
         %end;
         _cgrp
         into: _grplist separated by ',',
             : _dummy
         from _shldata
         where &class is not missing
         order by _cgrp;
      quit;
   %end;
   %else %do;
      %put ==> Alert! The class variable &class does not have a treatment group as you specified: &trtgrp;
      %put +++        Sorry, I can%str(%')t do any further analysis;
      %goto finish;
   %end;
%end;

%********************;
%do _i_=1 %to &_grpn;
   %let _grp&_i_=%trim(%left(%qscan(%quote(&_grplist), &_i_, %str(,))));
%end;
%********************;

%if (%quote(&trtgrp) eq) %then %do;
   data _hldata(rename=(_cgrp=&class));
      set _shldata;
      %if &_varchk=1 %then %do;
         %do _i_=1 %to &_grpn;
         if &class=&&_grp&_i_ then _cgrp=&_i_;
         %end;
      %end;
      %else %do;
         %do _i_=1 %to &_grpn;
         if (index(upcase(&class),"%trim(%left(&&_grp&_i_))")) then _cgrp=&_i_;
         %end;
      %end;
      drop &class;
   run;
%end;
%else %do;
   data _hldata(rename=(_cgrp=&class));
      set _shldata;
      drop &class;
   run;
%end;
/* For Unpaired case: count the maximum number of subjects of the two groups */
/* For Paired case: count the number of matched subjects in each group */
%let _minimumn=0;
proc sql noprint;
   select max(totobs) into: _maxn
   from (select count(*) as totobs
         from _hldata
         group by &class);

   select min(totobs) into: _minimumn
   from (select count(*) as totobs
         from _hldata
         group by &class);
quit;
%if &_minimumn <10 %then %do;
   %put ==> Note: Sample size is extremely small, do not trust the P-value in the output, which was;
   %put +++       calculated using large sample approximation. In order by get a relatively accurate;
   %put +++       p-value, please compare the calculated statistics provided in the output with the;
   %put +++       table given in book "Nonparmetric Statistical Methods" (Hollander M and Wolfe DA).;
%end;
%else %if &_minimumn <30 %then %do;
   %put ==> Note: Sample size is relatively small, P-value given in the output is calcualted using;
   %put +++       large sample approximation, so use it carefully. But you can manually compare the;
   %put +++       calculated statistics provided in the output with the table given in book;
   %put +++       "Nonparmetric Statistical Methods" (Hollander M and Wolfe DA).;
%end;
%else %do;
   %put ===> Note: the nonparametric analysis is carried out using large sample approprimation, so;
   %put +++        be careful about the P-value given in the output.;
%end;
%if (%index(%quote(%upcase(&option)), UNPAIR)) %then %do;
   %let _op=Unpaired;
   %if (%index(%quote(%upcase(&tiesadj)), T)) or (%quote(&tiesadj) eq 1) %then %do;
      %put ==> Alert! Option "Ties Adjustment" isn%str(%')t for Unpaired 2-sample locaiton analysis. Ties won%str(%')t;
      %put +++        be adjusted. Sorry for the inconvenience!;
   %end;
   proc ttest data=_hldata;
      var &avar;
      class &class;
      title1 "T-Test of Means (%trim(%left(&_op))), Group 1 vs Group 2";
   run;
   title;
   data _null_;
      file print;
      put &_linesize*'_';
   run;
   proc npar1way wilcoxon data=_hldata;
      var &avar;
      class &class;
      title1 "Wilcoxon Rank-Sum Test  (%trim(%left(&_op)))";
   run;
   title;
   data _hldata(keep=_diff);
      set _hldata end=last;
   *;
      array _ng(2)       _temporary_;
      array _av(2,&_maxn) _temporary_;
      retain _ng 0 _av;
   *;
      i=&class;
      _ng{i}=_ng{i}+1;
      _av(i,_ng{i})=&avar;
   *;
      if (last) then do;
         do j1=1 to _ng{2};
           do j2=1 to _ng{1};
              _diff=_av{2,j1}-_av{1,j2};
              output;
           end;
         end;
   *
   *  Determine order statistics for lower and upper bounds of the
   *  confidence interval using the method of Moses.
   *;
         _m=_ng{1};
         _n=_ng{2};
         %if (&tail eq 2) or (%index(%quote(%upcase(&tail)),TWO)) %then %do;
            _za=probit(1-&alpha/2);
            _ca=round(_m*_n/2-_za*sqrt(_m*_n*(_m+_n+1)/12),1);
            _lcl=_ca;
            _ucl=_m*_n+1-_ca;
            call symput("_lcl",_lcl);
            call symput("_ucl",_ucl);
         %end;
         %else %if (%quote(&tail) eq %quote(1)) or (%index(%quote(%upcase(&tail)),ONE)) %then %do;
            _za=probit(1-&alpha);
            _ca=round(_m*_n/2-_za*sqrt(_m*_n*(_m+_n+1)/12),1);
            %if (%index(%substr(%quote(%upcase(%trim(%left(&bound)))),1,3), %quote(L))) or
                (%index(%quote(%upcase(&bound)), %quote(LOW))) or
                (%index(%quote(%upcase(&bound)), %quote(BOTH))) or
                (%quote(&bound) eq) or (%quote(&tail) ne %quote(2)) %then %do;
               _lcl=_ca;
               call symput("_lcl",_lcl);
            %end;
            %if (%index(%substr(%quote(%upcase(%trim(%left(&bound)))),1,3), %quote(U))) or
                (%index(%quote(%upcase(&bound)), %quote(UP))) or
                (%index(%quote(%upcase(&bound)), %quote(BOTH))) or
                (%quote(&bound) eq) or (%quote(&tail) ne %quote(2)) %then %do;
               _ucl=_m*_n+1-_ca;
               call symput("_ucl",_ucl);
            %end;
         %end;
         %else %do;
            %put ==> Alert! I can take either one-sided or two-sided test:;
            %put            "&tail" isn%str(%')t a valid option;
            %goto finish;
         %end;
      end;
   run;
   /* Estimate the Median of the Walsh Average */
   proc means data=_hldata noprint;
      var _diff;
      output out=_hlestimates1 n=_n mean=_mean median=_median min=_min max=_max;
   run;
   title;
   proc sql noprint;
      select _median into: _mwalsh
      from _hlestimates1;
   quit;
   proc sort data=_hldata;
      by _diff;
   run;
   data _tmp1;
      file print;
      set _hldata end=lastone;
      retain _lconl _uconl .;
      if (_n_ eq 1) then do;
         put &_linesize*'_';
         put //  +5 "Distribution-free confidence interval based on Wilcoxon rank sum test using"
             /   +5 "the large sample approximation to the method of Moses (&_op Samples)"
             /   +5 "(Reference: Hollander M and Wolfe DA, 'Nonparametric Statistical Methods' pp 78-82)";
         %if (%quote(&tail) eq %quote(2)) or (%index(%upcase(&tail),TWO)) %then %do;
         put /   +5 %if &_varchk=1 %then %do; "Two Sided Test on Group &_grp2-&_grp1: "     %end;
                    %else %do;                "Two Sided Test on Group '&_grp2'-'&_grp1': " %end;
             //  +5 "H0: treatment = 0 vs H1: treatment <> 0;";
         %end;
         %else %if (%quote(&tail) eq %quote(1)) or (%index(%upcase(&tail),ONE)) %then %do;
         put /   +5 %if &_varchk=1 %then %do; "One Sided Test on Group &_grp2-&_grp1:"     %end;
                    %else %do;                "One Sided Test on Group '&_grp2'-'&_grp1':" %end;
             //  +5 "H0: treatment = 0 vs H1: treatment < 0 (or H1: treatment > 0);";
         %end;
         put // +11 "Median of Walsh Averages   = %trim(%left(&_mwalsh))" /;
      end;
      if (_n_ eq &_lcl) then do;
         %if (%index(%substr(%quote(%upcase(%trim(%left(&bound)))),1,3), %quote(L))) or
             (%index(%quote(%upcase(&bound)), %quote(LOW))) or (%quote(&tail) eq %quote(2)) %then %do;
         put +11 "Lower %sysevalf((1-&alpha)*100)% confidence bound = " _diff /;
         _lconl=_diff;
         keep _lconl;
         label _lconl="Lower Confidence Interval";
         %end;
      end;
      else if (_n_ eq &_ucl) then do;
         %if (%index(%substr(%quote(%upcase(%trim(%left(&bound)))),1,3), %quote(U))) or
             (%index(%quote(%upcase(&bound)), %quote(UP))) or (%quote(&tail) eq %quote(2)) %then %do;
         put  +11 "Upper %sysevalf((1-&alpha)*100)% confidence bound = " _diff;
         _uconl=_diff;
         keep _uconl;
         label _uconl="Upper Confidence Interval";
         %end;
      end;
      if lastone then do;
         output;
         put &_linesize*'_';
      end;
   run;
   title;
   proc sql;
      create table _tmp1 as
      select h.*,
             m._mean label="Average of Group Differences",
             m._median label="Hodges-Lehmann Estimator for Group Differences",
             m._min label="Minimum of of Group Differences",
             m._max label="Maximum of Group Differences"
      from _tmp1 as h, _hlestimates1 as m;
   quit;
   proc print data=_tmp1 label noobs;
   title "Nonparametric Analysis for Unpaired 2-Sample Locations Differences";
   run;
%end;
%else %if (%index(%quote(%upcase(&option)), PAIR)) and (not %index(%quote(%upcase(&option)), UN)) %then %do;
   %let _op=Paired; %let _byn=1; %let _bycnt=1;
   %let _by1=%qscan(&matchby, &_byn, %str( ,()));
   %do %while(%length(&&_by&_byn) gt 0);
      %let _byn=%eval(&_byn+1);
      %let _by&_byn=%qscan(&matchby, &_byn, %str( ,()));
   %end;
   %let _byn =%eval(&_byn-1);
   proc sql noprint;
      select min(totobs) into: _minn
      from (select count(*) as totobs
            from (select distinct %do _i_=1 %to &_byn; &&_by&_i_, %end; &class
                  from _hldata)
            group by &class);
   quit;
   %if &_minn ne &_maxn %then %do;
      %put ==> Alert! The 2 groups of subjects are not matched, or there may be duplicate records%str(%;);
      %put +++        since the number of observations in the larger group (%trim(%left(&_maxn))) <> the number;
      %put +++        of subjects in the smaller group (%trim(%left(&_minn))). Please make sure the 2 group of;
      %put +++        subjects are matched!;
      %goto finish;
   %end;
   %if (%quote(&theta0) eq) %then %do;
      %put ==> Alert! I need a treatment estimator (theta0) for the null hypothesis: H0: treatment - control=%trim(%left(&theta0))%str(%;);
      %put +++        I assume you want to compare the treatment effect is 0 (theta0=0), otherwise, assign a different;
      %put +++        theta0.;
      %let theta0=0;
   %end;
   proc sql;
      create table _phldata as
      select %do _i_=1 %to &_byn; g1.%trim(%left(&&_by&_i_)), %end;
             g2.%trim(%left(&avar))-g1.%trim(%left(&avar)) as _z,
             count(*) as _n,
             (g2.%trim(%left(&avar))-g1.%trim(%left(&avar))-&theta0) as _diff,
             abs(g2.%trim(%left(&avar))-g1.%trim(%left(&avar))-&theta0) as _abdiff,
             ((g2.%trim(%left(&avar))-g1.%trim(%left(&avar))-&theta0)>0) as _phi
      from (select distinct %do _i_=1 %to &_byn; &&_by&_i_, %end; &class, &avar
            from _hldata
            where &class=1) as g1,
           (select distinct %do _i_=1 %to &_byn; &&_by&_i_, %end; &class, &avar
            from _hldata
            where &class=2) as g2
      where g1.%trim(%left(&_by1))=g2.%trim(%left(&_by1))
                     %if &_byn ge 2 %then %do;
                        %do _i_=2 %to &_byn;
                           and g1.%trim(%left(&&_by&_i_))=g2.%trim(%left(&&_by&_i_))
                        %end;
                     %end;
            %if (%index(%quote(%upcase(&tiesadj)), T)) or (%quote(&tiesadj) eq 1) %then %do;
               and (g2.%trim(%left(&avar))-g1.%trim(%left(&avar))-&theta0) ne 0
            %end;;
   quit;
   proc ttest data=_phldata;
      var _diff;
      %if &_varchk=1 %then %do;
      title1 "T-Test of Means (%trim(%left(&_op))) (H0: Group %trim(%left(&_grp2))-%trim(%left(&_grp1))=%trim(%left(&theta0)))";
      %end;
      %else %do;
      title1 "T-Test of Means (%trim(%left(&_op))) (H0: Group '%trim(%left(&_grp2))'-'%trim(%left(&_grp1))'=%trim(%left(&theta0)))";
      %end;
   run;
   title;
   proc rank data=_phldata out=_phldata;
   var _abdiff;
   ranks _ranka;
   run;
   data _hlestimates1;
      set _phldata end=lastobs;
      retain _wp 0;
      _wp=_wp+_ranka*_phi;
      if lastobs then do;
         _uhead=(_wp-_n*(_n+1)/4)/sqrt(_n*(_n+1)*(2*_n+1)/24);
         %if (%quote(&tail) eq %quote(2)) or (%index(%quote(%upcase(&tail)),TWO)) %then %do;
/*            _za=probit(1-&alpha/2);*/_za=tinv((1-&alpha/2),_n);
            _pvalue=(1-probnorm(abs(_uhead)))*2;
            _ca=_n*(_n+1)/4+1-_za*sqrt(_n*(_n+1)*(2*_n+1)/24);
            _lcl=round(_ca,1);
            _ucl=round(_n*(_n+1)/4+_za*sqrt(_n*(_n+1)*(2*_n+1)/24),1);
            call symput("_lcl",_lcl);
            call symput("_ucl",_ucl);
         %end;
         %else %if (%quote(&tail) eq %quote(1)) or (%index(%quote(%upcase(&tail)),ONE)) %then %do;
            /*_za=probit(1-&alpha);*/_za=tinv((1-&alpha/2),_n);
            _pvalue=(1-probnorm(abs(_uhead)));
            %if (%index(%substr(%quote(%upcase(%trim(%left(&bound)))),1,3), %quote(L))) or
                (%index(%quote(%upcase(&bound)), %quote(LOW))) or
                (%index(%quote(%upcase(&bound)), %quote(BOTH))) or
                (%quote(&bound) eq) or (%quote(&tail) ne %quote(2)) %then %do;
               _lcl=round(_n*(_n+1)/4+1-_za*sqrt(_n*(_n+1)*(2*_n+1)/24),1);
               call symput("_lcl",_lcl);
            %end;
            %if (%index(%substr(%quote(%upcase(%trim(%left(&bound)))),1,3), %quote(U))) or
                (%index(%quote(%upcase(&bound)), %quote(UP))) or
                (%index(%quote(%upcase(&bound)), %quote(BOTH))) or
                (%quote(&bound) eq) or (%quote(&tail) ne %quote(2)) %then %do;
               _ucl=round(_n*(_n+1)/4+_za*sqrt(_n*(_n+1)*(2*_n+1)/24),1);
               call symput("_ucl",_ucl);
            %end;
         %end;
         %else %do;
            %put ==> Alert! I can take either one-sided or two-sided test:;
            %put            "&tail" isn%str(%')t a valid option;
            %goto finish;
         %end;
         output;
      end;
   run;
   proc sql;
      create table _whldata as
      select (t1._z1+t2._z2)/2 as _walsh
      from (select _z as _z1, _n as _n1
            from _phldata) as t1,
            (select _z as _z2, _n as _n2
             from _phldata) as t2
      where _n1<=_n2
      order by _walsh;
   quit;
   proc means data=_whldata noprint;
      var _walsh;
      output out=_hlestimates2 mean=_mean median=_median min=_min max=_max;
   run;
   title;
   proc sql noprint;
      select h1._uhead, h1._pvalue, h2._median into: _uhead, :_pvalue, :_mwalsh
      from _hlestimates1 as h1, _hlestimates2 as h2;
   quit;
   data _hlestimates3;
      file print;
      set _whldata end=lastobs;
      retain _lconl _uconl;
      if _n_=1 then do;
         put &_linesize*'_';
         put //  +5 'Hepothesis Test For Paired Two-Sample Location Differences With Equal Variances using'
             /   +5 'large sample approximation and Ties Adjustment with Signed-Rank Procedure.'
             /   +5 '(Reference:  Hollander M and Wolfe DA,"Nonparametric Statistical Methods," pp ??-??)';
      end;
      %if (%quote(&tail) eq %quote(2)) or (%index(%quote(%upcase(&tail)),TWO)) %then %do;
         if (_n_ eq &_lcl) then do;
            put / +5   %if &_varchk=1 %then %do; "Two Sided Test: H0: Group %trim(%left(&_grp2))-%trim(%left(&_grp1))=%trim(%left(&theta0)) vs"
                                          / +5   "                H1: Group %trim(%left(&_grp2))-%trim(%left(&_grp1))<>%trim(%left(&theta0));" %end;
                       %else %do;                "Two Sided Test: H0: Group '%trim(%left(&_grp2))'-'%trim(%left(&_grp1))'=%trim(%left(&theta0)) vs"
                                          / +5   "                H1: Group '%trim(%left(&_grp2))'-'%trim(%left(&_grp1))'<>%trim(%left(&theta0));" %end;;
            put // +12 "Median of Walsh Averages   = %trim(%left(&_mwalsh))" ;
            put / +26 "Statistics   = %trim(%left(&_uhead))";
            put / +31 "P-value = %trim(%left(&_pvalue))";
            _lconl=_walsh;
            put / +10 "Lower %sysevalf((1-&alpha)*100)% confidence bound = " _lconl;
         end;
         else if (_n_ eq &_ucl) then do;
            _uconl=_walsh;
            put / +10 "Upper %sysevalf((1-&alpha)*100)% confidence bound = " _uconl;
         end;
         keep _lconl _uconl;
         label _lconl="Lower Confidence Bound"
               _uconl="Upper Confidence Bound";
      %end;
      %else %if (%quote(&tail) eq %quote(1)) or (%index(%quote(%upcase(&tail)),ONE)) %then %do;
         %if (%index(%substr(%quote(%upcase(%trim(%left(&bound)))),1,3), %quote(L))) or
             (%index(%quote(%upcase(&bound)), %quote(LOW))) or
             (%index(%quote(%upcase(&bound)), %quote(BOTH))) or
             (%quote(&bound) eq) or (%quote(&tail) ne %quote(2)) %then %do;
            if (_n_ eq &_lcl) then do;
               put / +5   %if &_varchk=1 %then %do; "One Sided Test: H0: Group %trim(%left(&_grp2))-%trim(%left(&_grp1))=%trim(%left(&theta0)) vs"
                                             / +5   "                H1: Group %trim(%left(&_grp2))-%trim(%left(&_grp1))>%trim(%left(&theta0));"; %end;
                          %else %do;                "One Sided Test: H0: Group '%trim(%left(&_grp2))'-'%trim(%left(&_grp1))'=%trim(%left(&theta0)) vs"
                                             / +5   "                H1: Group '%trim(%left(&_grp2))'-'%trim(%left(&_grp1))'>%trim(%left(&theta0));"; %end;
               put // +12 "Median of Walsh Averages   = %trim(%left(&_mwalsh))";
               put / +26 "Statistics   = %trim(%left(&_uhead))";
               put / +31 "P-value = = %trim(%left(&_pvalue))" ;
               _lconl=_walsh;
               put / +10 "Lower %sysevalf((1-&alpha)*100)% confidence bound = " _lconl;
            end;
            keep _uhead _lconl;
            label _uhead="Statistics" _lconl="Lower Confidence Bound";
         %end;
         %if (%index(%substr(%quote(%upcase(%trim(%left(&bound)))),1,3), %quote(U))) or
             (%index(%quote(%upcase(&bound)), %quote(UP))) or
             (%index(%quote(%upcase(&bound)), %quote(BOTH))) or
             (%quote(&bound) eq) or (%quote(&tail) ne %quote(2)) %then %do;
            put / +5   %if &_varchk=1 %then %do; "One Sided Test: H0: Group %trim(%left(&_grp2))-%trim(%left(&_grp1))=%trim(%left(&theta0)) vs"
                                          / +5   "                H1: Group %trim(%left(&_grp2))-%trim(%left(&_grp1))<%trim(%left(&theta0));"; %end;
                       %else %do;                "One Sided Test: H0: Group '%trim(%left(&_grp2))'-'%trim(%left(&_grp1))'=%trim(%left(&theta0)) vs"
                                          / +5   "                H1: Group '%trim(%left(&_grp2))'-'%trim(%left(&_grp1))'<%trim(%left(&theta0));"; %end;
            put // +12 "Median of Walsh Averages   = %trim(%left(&_mwalsh))";
            put / +26 "Statistics   = %trim(%left(&_uhead))";
            put / +31 "P-value = = %trim(%left(&_pvalue))" ;
            if (_n_ eq &_ucl) then do;
               _uconl=_walsh;
               put / +10 "Upper %sysevalf((1-&alpha)*100)% confidence bound = " _uconl;
            end;
            keep _uconl;
            label  _uconl="Upper Confidence Bound";
         %end;
      %end;
      %else %do;
         %put ==> Alert! I can take either one-sided or two-sided test:;
         %put            "&tail" isn%str(%')t a valid option;
         %goto finish;
      %end;
      if lastobs then do;
         output;
         put &_linesize*'_';
      end;
   run;
   proc sql noprint;
      create table _tmp1 as
      select h1._uhead label="Statistics",
             h1._pvalue label="P-value",
             h2._mean label="Mean of Walsh Averages",
             h2._median label="Hodges-Lehmann Estimator for Group Differences",
             h2._min label="Mininum of Walsh Averages",
             h2._max label="Maximum of Walsh Averages",
             h3.*
      from _hlestimates1 as h1, _hlestimates2 as h2, _hlestimates3 as h3;
   quit;
   proc print data=_tmp1 label noobs;
   title "Nonparametric Analysis for Paired 2-Sample Locations Differences";
   run;
   proc datasets library=work nolist;
        delete _phldata _whldata _hlestimates1 _hlestimates2 _hlestimates3;
   run;quit;
%end;
title;
data _null_;
   file print;
   put &_linesize*'_';
run;
%if (%quote(&outdata) ne) %then %do;
data &outdata;
   set _tmp1;
run;
%end;
%else %let syslast=&_tmplast_;
proc datasets library=work nolist;
     delete _vchecktmp _shldata _tmp1 _hldata;
run;quit;
%finish:
run;quit;
options FORMDLIM="ƒ";
%mend npar2mean;